home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / brklyprl.lha / Comp / herve_peephole.pl < prev    next >
Text File  |  1989-04-14  |  7KB  |  191 lines

  1.  
  2. /* Copyright (C) 1988, 1989 Herve' Touati, Aquarius Project, UC Berkeley */
  3.  
  4. /* Copyright Herve' Touati, Aquarius Project, UC Berkeley */
  5.  
  6. % does the following modifications:
  7. % (1) add an arg to unify structures to specify read or unknown mode
  8. % we will make it general. If unbound, means the mode is unknown
  9. % have to modify the write routines accordingly
  10. % (2) add the arity to the get_structure and put_structure instructions
  11. % (3) insert, between two unify instructions, in a list context, the
  12. % instruction get_cdr_list, with no arguments.
  13. % (4) fix up the treatment of metacalls
  14. % It works in two passes:
  15. % the first pass unroll the unify_voids, and propagates the read and
  16. % unknown modes.  
  17. % the second pass treats the lists.
  18. % the third pass replaces the allocates N into inits and removes most
  19. % of the inits.     
  20.  
  21. herve_peephole(Code,PCode,Link) :-
  22.     herve_first_pass(Code,ICode,[],unknown),
  23.     herve_second_pass(ICode,SCode,[],unknown),
  24.     herve_third_pass(SCode,PCode,Link).
  25.  
  26. herve_first_pass([Instr|Code],[Instr|PCode],Link,_) :-
  27.     (Instr = get_list(_); Instr = get(structure,_,_)),
  28.     !,
  29.     herve_first_pass(Code,PCode,Link,unknown).
  30.  
  31. herve_first_pass([Instr|Code],[Instr|PCode],Link,_) :-
  32.     (Instr = put_list(_); Instr = put(structure,_,_)),
  33.     !,
  34.     herve_first_pass(Code,PCode,Link,write).
  35.  
  36. herve_first_pass([unify(void,N)|Code],[unify(void,1,Mode)|PCode],Link,Mode) :-
  37.     N > 1,
  38.     !,
  39.     N1 is N - 1,
  40.     herve_first_pass([unify(void,N1)|Code],PCode,Link,Mode).
  41.  
  42. herve_first_pass([unify(Type,X)|Code],[unify(Type,X,Mode)|PCode],Link,Mode) :-
  43.     !,
  44.     herve_first_pass(Code,PCode,Link,Mode).
  45.  
  46. herve_first_pass([unify_nil|Code],[unify_nil(Mode)|PCode],Link,Mode) :-
  47.     !,
  48.     herve_first_pass(Code,PCode,Link,Mode).
  49.  
  50. % last instruction
  51. herve_first_pass([],LastCode,LastCode,_).
  52.  
  53. % catch all case
  54. herve_first_pass([Instr|Code],[Instr|PCode],Link,Mode) :-
  55.     !,
  56.     herve_first_pass(Code,PCode,Link,Mode).
  57.  
  58. herve_second_pass([Instr|Code],[Instr|PCode],Link,_) :-
  59.     (Instr = get_list(_); Instr = put_list(_)),
  60.     !,
  61.     skip_allocate(Code,Rest,PCode,PRest),
  62.     herve_second_pass(Rest,PRest,Link,list).
  63.  
  64. herve_second_pass([Instr|Code],[Instr|PCode],Link,_) :-
  65.     (Instr = put(structure,_,_); Instr = get(structure,_,_)),
  66.     !,
  67.     herve_second_pass(Code,PCode,Link,structure).
  68.  
  69. herve_second_pass([unify(cdr,X,Mode)|Code],PCode,Link,Context) :-
  70.     !,
  71.     PCode = [unify(variable,X,Mode)|Rest],
  72.     herve_second_pass(Code,Rest,Link,Context).
  73.  
  74. herve_second_pass([allocate(0)|Code],PCode,Link,Context) :-
  75.     !,
  76.     herve_second_pass(Code,PCode,Link,Context).
  77.  
  78. herve_second_pass([Instr|Code],[get_cdr_list(Mode),Instr|PCode],Link,list) :-
  79.     Instr = unify(_,_,Mode),
  80.     !,
  81.     herve_second_pass(Code,PCode,Link,list).
  82.  
  83. herve_second_pass([unify_nil(_)|Code],PCode,Link,structure) :-
  84.     !,
  85.     herve_second_pass(Code,PCode,Link,structure).
  86.  
  87. herve_second_pass([Instr|Code],[Instr|PCode],Link,structure) :-
  88.     Instr = unify(_,_,_),
  89.     !,
  90.     herve_second_pass(Code,PCode,Link,structure).
  91.  
  92. % last instruction
  93. herve_second_pass([],LastCode,LastCode,_).
  94.  
  95. % catch-all case
  96. herve_second_pass([Instr|Code],[Instr|PCode],Link,Context) :-
  97.     !,
  98.     herve_second_pass(Code,PCode,Link,Context).
  99.  
  100. skip_allocate([allocate(N),Instr|Rest],Rest,PCode,PRest) :-
  101.     !,
  102.     PCode = [allocate(N),Instr|PRest].
  103. skip_allocate([Instr|Rest],Rest,[Instr|PRest],PRest).    
  104.  
  105. % treats the allocates correctly. Replaces them by inits, and only put
  106. % the necessary number of inits. Also look at the first occurrence of
  107. % those variables in the remaining of the clause, and replace their
  108. % variable annotations by value annotations.
  109.  
  110. % Rest = a list of instructions, [] terminated, corresponding to a clause
  111. % PCode = the transformed of Rest
  112. % Link = the link to the end of PCode
  113. herve_third_pass(Rest,PCode,Link) :-
  114.     herve_third_pass(Rest,PCode,Link,_,[],noalloc).
  115.  
  116. % 4th argument = place holder: [PLink,N|PRest]
  117. % PLink = location in the code for the sequence of inits
  118. % N = size of env
  119. % PRest = the rest of the code
  120. % 5th argument = the list of Yvars encountered so far (before first jump)
  121. % 6th argument = whether an allocate has been encountered so far or not
  122. herve_third_pass([allocate(N)|Rest],PLink,Link,_,YVars,_) :- !,
  123.     herve_third_pass(Rest,PRest,Link,[PLink,N|PRest],YVars,alloc).
  124. herve_third_pass([Instr|Rest],[Instr|PRest],Link,X,YVars,Mode) :-
  125.     Instr = unify(variable,y(N),_), !,
  126.     herve_third_pass(Rest,PRest,Link,X,[y(N)|YVars],Mode).
  127. herve_third_pass([Instr|Rest],[Instr|PRest],Link,X,YVars,Mode) :-
  128.     Instr =.. [Name,variable,y(N)|_], !,
  129.     (Name = get; Name = put),
  130.     herve_third_pass(Rest,PRest,Link,X,[y(N)|YVars],Mode).
  131. herve_third_pass([Instr|Rest],[Instr|PRest],Link,X,YVars,alloc) :-
  132.     (Instr = call(_,_); Instr = execute(_); 
  133.         Instr = proceed; Instr = fail/0), !,
  134.     compute_inits(X,YVars,InitVars),
  135.     herve_end_third_pass(Rest,PRest,Link,InitVars).
  136. herve_third_pass([Instr|Code],[Instr|PCode],Link,Init,YVars,Mode) :-
  137.     herve_third_pass(Code,PCode,Link,Init,YVars,Mode).
  138. herve_third_pass([],Link,Link,_,_,_).
  139.  
  140. % Marker = pointer to the place in the code where to put the inits
  141. % Rest = link to the end of the inits
  142. % N = size of the environment
  143. % YVars = list of the variables encountered before the first jump
  144. % InitVars = list of the variables to be initialized
  145. % does the insertion of the init code.
  146. compute_inits([Marker,N|Rest],YVars,InitVars) :-
  147.     compute_complement(N,YVars,InitVars),
  148.     make_inits(InitVars,Inits,ILink),
  149.     Marker = Inits,
  150.     ILink = Rest.
  151.  
  152. % replace [y(1),y(2)] by [init(1),init(2)|Link]
  153. make_inits([],Link,Link).
  154. make_inits([y(N)|YVars],[init(N)|Inits],Link) :-
  155.     make_inits(YVars,Inits,Link).
  156.  
  157. % y(I) is in InitVars iff 1 <= I <= N and y(I) is not in YVars
  158. compute_complement(0,_,[]) :- !.
  159. compute_complement(N,YVars,InitVars) :-
  160.     member(y(N),YVars), !,
  161.     N1 is N - 1,
  162.     compute_complement(N1,YVars,InitVars).
  163. compute_complement(N,YVars,[y(N)|InitVars]) :-
  164.     N1 is N - 1,
  165.     compute_complement(N1,YVars,InitVars).
  166.  
  167. % replace first encounter of a Y variable after an init from variable
  168. % to value annotation
  169. herve_end_third_pass([Instr|Rest],[NewInstr|PRest],Link,InitVars) :-
  170.     Instr = unify(variable,y(N),X), !,
  171.     (match_and_remove(y(N),InitVars,NewInitVars) ->
  172.         NewInstr = unify(value,y(N),X);
  173.         (NewInstr = Instr, NewInitVars = InitVars)),
  174.         herve_end_third_pass(Rest,PRest,Link,NewInitVars).
  175. herve_end_third_pass([Instr|Rest],[NewInstr|PRest],Link,InitVars) :-
  176.     Instr =.. [Name,variable,y(N)|Tail],
  177.     (Name = get; Name = put), !,
  178.     (match_and_remove(y(N),InitVars,NewInitVars) ->
  179.         NewInstr =.. [Name,value,y(N)|Tail];
  180.         (NewInstr = Instr, NewInitVars = InitVars)),
  181.     herve_end_third_pass(Rest,PRest,Link,NewInitVars).
  182. herve_end_third_pass([Instr|Code],[Instr|PCode],Link,InitVars) :- !,
  183.     herve_end_third_pass(Code,PCode,Link,InitVars).
  184. herve_end_third_pass([],LastCode,LastCode,_).
  185.  
  186. % fail if 1st argument does not belong to 2nd argument
  187. % when succeeds, the 3rd argument is the 2nd minus the first.
  188. match_and_remove(Y,[Y|Inits],Inits) :- !.
  189. match_and_remove(Y,[Z|Inits],[Z|NewInits]) :- 
  190.     match_and_remove(Y,Inits,NewInits).
  191.